DomainInit Subroutine

public subroutine DomainInit(inifile)

Load domain properties

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: inifile

name of configuration file


Variables

Type Visibility Attributes Name Initial
integer(kind=short), public :: option

Source Code

SUBROUTINE DomainInit &
!
( inifile )

IMPLICIT NONE

! arguments with intent (in)

CHARACTER (LEN = *), INTENT(IN) :: inifile  !!name of configuration file

!  local declarations
INTEGER (KIND = short) :: option

!-------------------------end of declarations----------------------------------

!open and load configuration file
CALL IniOpen (inifile, domainini)

!read domain mask
IF (SectionIsPresent('mask', domainini)) THEN
  CALL GridByIni (domainini, mask, section = 'mask')
  mask_loaded = .TRUE.
ELSE !basin is mandatory: stop the program
   CALL Catch ('error', 'DomainProperties',   &
			   'error in loading mask: ' ,  &
			    argument = 'section not defined in ini file' )
END IF


!read albedo
IF (SectionIsPresent('albedo', domainini)) THEN
  CALL GridByIni (domainini, albedoGround, section = 'albedo')
  
  IF  ( .NOT. CRSisEqual (mask = mask, grid = albedoGround, &
        checkCells = .TRUE.) ) THEN
       CALL Catch ('error', 'DomainProperties',   &
			    'wrong spatial reference in albedo' )
  END IF
  
   
  !initialise albedo state variable as albedoGround
  CALL NewGrid (albedo, albedoGround)
  
  albedo_loaded = .TRUE.
END IF


!read land cover
IF (SectionIsPresent('land-cover', domainini)) THEN
  CALL GridByIni (domainini, landcover, section = 'land-cover')
  IF  ( .NOT. CRSisEqual (mask = mask, grid = landcover, &
        checkCells = .TRUE.) ) THEN
       CALL Catch ('error', 'DomainProperties',   &
			    'wrong spatial reference in land cover' )
  END IF
  landcover_loaded = .TRUE.
END IF


!read soil texture
IF (SectionIsPresent('soil-texture', domainini)) THEN
    CALL GridByIni (domainini, soilTexture, section = 'soil-texture')
    IF  ( .NOT. CRSisEqual (mask = mask, grid = soilTexture, &
          checkCells = .TRUE.) ) THEN
        CALL Catch ('error', 'DomainProperties',   &
			    'wrong spatial reference in soil texture' )
    END IF
    soil_texture_loaded = .TRUE.
END IF
  

!compute centroid of mask  
CALL Centroid (mask, point1)
       
point2 % system = DecodeEPSG (4326)
       
CALL Convert (point1, point2)
       
latCentroid = point2 % northing
       
latCentroid = latCentroid * degToRad


!close ini
CALL IniClose (domainini)

RETURN
END SUBROUTINE DomainInit